InitSpatialAverageCanopy Subroutine

public subroutine InitSpatialAverageCanopy(fileini, pathout, canopyStorage, throughfall, pt)

Initialization of spatial average of canopy interception variables

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: fileini
character(len=*), intent(in) :: pathout
type(grid_real), intent(in) :: canopyStorage

water canopy storage (mm)

type(grid_real), intent(in) :: throughfall

effective rain reaching soil surface (m/s)

type(grid_real), intent(in) :: pt

potential transpiration from canopy (m/s)


Variables

Type Visibility Attributes Name Initial
type(IniList), public :: iniDB

Source Code

SUBROUTINE InitSpatialAverageCanopy   & 
!
 (fileini, pathout, canopyStorage, throughfall,  pt)  

IMPLICIT NONE

!arguments with intent in:
CHARACTER(LEN = *), INTENT(IN)    :: fileini 
CHARACTER(LEN = *), INTENT(IN)    :: pathout     
TYPE (grid_real), INTENT(IN) :: canopyStorage !!water canopy storage (mm)
TYPE (grid_real), INTENT(IN) :: throughfall !! effective rain reaching soil surface (m/s)
TYPE (grid_real), INTENT(IN) ::  pt!! potential transpiration from canopy (m/s)

!local declarations
TYPE(IniList)          :: iniDB
!-------------------------------end of declaration-----------------------------

!  open and read configuration file
CALL IniOpen (fileini, iniDB) 

! search for active variable for output
CALL Catch ('info', 'SpatialAverage', 'checking for canopy active variables ')

countcanopy = 0

!canopy storage
IF ( IniReadInt ('canopy-storage', iniDB, section = 'canopy') == 1) THEN
   IF ( .NOT. ALLOCATED (canopyStorage % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'canopy storage not allocated, &
                                            forced to not export spatial average ')
       canopyout (1) = .FALSE.
   ELSE
       canopyout (1) = .TRUE.
       countcanopy = countcanopy + 1
   END IF
ELSE
   canopyout (1) = .FALSE.
END IF

!throughfall
IF ( IniReadInt ('throughfall', iniDB, section = 'canopy') == 1) THEN
   IF ( .NOT. ALLOCATED (throughfall % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'throughfall not allocated, &
                                            forced to not export spatial average ')
       canopyout (2) = .FALSE.
   ELSE
       canopyout (2) = .TRUE.
       countcanopy = countcanopy + 1
   END IF
ELSE
   canopyout (2) = .FALSE.
END IF


!canopy evaporation
IF ( IniReadInt ('transpiration', iniDB, section = 'canopy') == 1) THEN
   IF ( .NOT. ALLOCATED (pt % mat) ) THEN
       CALL Catch ('warning', 'SpatialAverage', 'transpiration not allocated, &
                                            forced to not export spatial average ')
       canopyout (3) = .FALSE.
   ELSE
       canopyout (3) = .TRUE.
       countcanopy = countcanopy + 1
   END IF
ELSE
   canopyout (3) = .FALSE.
END IF

canopyInitialized = .TRUE.

CALL IniClose (iniDB) 

CALL ConfigureExtents (fileini, pathout)


RETURN
END SUBROUTINE InitSpatialAverageCanopy